home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / prolog / brklyprl.lha / Emulator / Tests / nand.pl < prev    next >
Encoding:
Text File  |  1989-04-14  |  19.3 KB  |  561 lines

  1.  
  2. /* Copyright (C) 1988, 1989 Herve' Touati, Aquarius Project, UC Berkeley */
  3.  
  4. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  5. %
  6. %  This is a rough approximation to the algorithm presented in:
  7. %
  8. %    "An Algorithm for NAND Decomposition Under Network Constraints,"
  9. %    IEEE Trans. Comp., vol C-18, no. 12, Dec. 1969, p. 1098
  10. %    by E. S. Davidson.
  11. %
  12. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  13. %
  14. %  I have used the paper's terminology for names used in the program.
  15. %
  16. %  The data structure for representing functions and variables is
  17. %        function(FunctionNumber, TrueSet, FalseSet,
  18. %            ConceivableInputs,
  19. %            ImmediatePredecessors, ImmediateSuccessors,
  20. %            Predecessors, Successors)
  21. %
  22. %
  23. %  Common names used in the program:
  24. %
  25. %    NumVars        number of variables (signal inputs)
  26. %    NumGs        current number of variables and functions
  27. %    Gs        list of variable and function data
  28. %    Gi,Gj,Gk,Gl    individual variable or function--letter corresponds to
  29. %            the subscript in the paper (most of the time)
  30. %    Vector,V    vector from a function's true set
  31. %
  32. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  33.  
  34. main :- main(0).
  35.  
  36. main(N) :-
  37.     init_state(N, NumVars, NumGs, Gs),
  38.     add_necessary_functions(NumVars, NumGs, Gs, NumGs2, Gs2),
  39.     test_bounds(NumVars, NumGs2, Gs2),
  40.     search(NumVars, NumGs2, Gs2).
  41. main(_) :-
  42.     write('Search completed'), nl.
  43.  
  44. %  Test input
  45. %  init_state(circuit(NumInputs, NumOutputs, FunctionList))
  46. init_state(0, 2, 3, [        % 2 input xor
  47.         function(2, [1,2], [0,3], [], [], [], [], []),
  48.         function(1, [2,3], [0,1], [], [], [], [], []),
  49.         function(0, [1,3], [0,2], [], [], [], [], [])
  50.         ]) :-
  51.     update_bounds(_, 100, _).
  52. init_state(1, 3, 4, [        % carry circuit
  53.         function(3, [3,5,6,7], [0,1,2,4], [], [], [], [], []),
  54.         function(2, [4,5,6,7], [0,1,2,3], [], [], [], [], []),
  55.         function(1, [2,3,6,7], [0,1,4,5], [], [], [], [], []),
  56.         function(0, [1,3,5,7], [0,2,4,6], [], [], [], [], [])
  57.         ]) :-
  58.     update_bounds(_, 100, _).
  59. init_state(2, 3, 4, [        % example in paper
  60.         function(3, [1,2,4,6,7], [0,3,5], [], [], [], [], []),
  61.         function(2, [4,5,6,7], [0,1,2,3], [], [], [], [], []),
  62.         function(1, [2,3,6,7], [0,1,4,5], [], [], [], [], []),
  63.         function(0, [1,3,5,7], [0,2,4,6], [], [], [], [], [])
  64.         ]) :-
  65.     update_bounds(_, 100, _).
  66. init_state(3, 3, 4, [        % sum (3 input xor)
  67.         function(3, [1,2,4,7], [0,3,5,6], [], [], [], [], []),
  68.         function(2, [4,5,6,7], [0,1,2,3], [], [], [], [], []),
  69.         function(1, [2,3,6,7], [0,1,4,5], [], [], [], [], []),
  70.         function(0, [1,3,5,7], [0,2,4,6], [], [], [], [], [])
  71.         ]) :-
  72.     update_bounds(_, 100, _).
  73. init_state(4, 3, 5, [        % do sum and carry together
  74.         function(4, [3,5,6,7], [0,1,2,4], [], [], [], [], []),
  75.         function(3, [1,2,4,7], [0,3,5,6], [], [], [], [], []),
  76.         function(2, [4,5,6,7], [0,1,2,3], [], [], [], [], []),
  77.         function(1, [2,3,6,7], [0,1,4,5], [], [], [], [], []),
  78.         function(0, [1,3,5,7], [0,2,4,6], [], [], [], [], [])
  79.         ]) :-
  80.     update_bounds(_, 100, _).
  81. init_state(5, 5, 8, [        % 2 bit full adder
  82.         function(7,        % A2 (output)
  83.             [1,3,4,6,9,11,12,14,16,18,21,23,24,26,29,31],
  84.             [0,2,5,7,8,10,13,15,17,19,20,22,25,27,28,30],
  85.             [], [], [], [], []),
  86.         function(6,        % B2 (output)
  87.             [2,3,5,6,8,9,12,15,17,18,20,21,24,27,30,31],
  88.             [0,1,4,7,10,11,13,14,16,19,22,23,25,26,28,29],
  89.             [], [], [], [], []),
  90.         function(5,        % carry-out (output)
  91.             [7,10,11,13,14,15,19,22,23,25,26,27,28,29,30,31],
  92.             [0,1,2,3,4,5,6,8,9,12,16,17,18,20,21,24],
  93.             [], [], [], [], []),
  94.         function(4,        % carry-in
  95.             [16,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31],
  96.             [0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15],
  97.             [], [], [], [], []),
  98.         function(3,        % B1 input
  99.             [8,9,10,11,12,13,14,15,24,25,26,27,28,29,30,31],
  100.             [0,1,2,3,4,5,6,7,16,17,18,19,20,21,22,23],
  101.             [], [], [], [], []),
  102.         function(2,        % B0 input
  103.             [4,5,6,7,12,13,14,15,20,21,22,23,28,29,30,31],
  104.             [0,1,2,3,8,9,10,11,16,17,18,19,24,25,26,27],
  105.             [], [], [], [], []),
  106.         function(1,         % A1 input
  107.             [2,3,6,7,10,11,14,15,18,19,22,23,26,27,30,31],
  108.             [0,1,4,5,8,9,12,13,16,17,20,21,24,25,28,29],
  109.             [], [], [], [], []),
  110.         function(0,        % A0 input
  111.             [1,3,5,7,9,11,13,15,17,19,21,23,25,27,29,31],
  112.             [0,2,4,6,8,10,12,14,16,18,20,22,24,26,28,30],
  113.             [], [], [], [], [])
  114.         ]) :-
  115.     update_bounds(_, 21, _).
  116.  
  117.  
  118. %  Iterate over all the TRUE vectors that need to be covered.
  119. %  If no vectors remain to be covered (select_vector fails), then
  120. %  the circuit is complete (printout results, update bounds, and
  121. %  continue search for a lower cost circuit).
  122. search(NumVars, NumGsIn, GsIn) :-
  123.     select_vector(NumVars, NumGsIn, GsIn, Gj, Vector), !,
  124.     cover_vector(NumVars, NumGsIn, GsIn, Gj, Vector, NumGs, Gs),
  125.     add_necessary_functions(NumVars, NumGs, Gs, NumGsOut, GsOut),
  126.     test_bounds(NumVars, NumGsOut, GsOut),
  127.     search(NumVars, NumGsOut, GsOut).
  128. search(NumVars, NumGs, Gs) :-
  129.     output_results(NumVars, NumGs, Gs),
  130.     update_bounds(NumVars, NumGs, Gs),
  131.     fail.
  132.  
  133. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  134. %  Given the current solution, pick the best uncovered TRUE vector
  135. %  for covering next.
  136. %  The selected vector is specified by its vector number and function.
  137. %  Select_vector fails if all TRUE vectors are covered.
  138. %  Select_vector is determinant (gives only one solution).
  139. select_vector(NumVars, NumGs, Gs, Gj, Vector) :-
  140.     select_vector(Gs, NumVars, NumGs, Gs,
  141.         dummy, 0, nf, 999, Gj, Vector, Type, _), !,
  142.     \+ Type = cov,
  143.     \+ Type = nf.
  144.  
  145. % loop over functions
  146. select_vector([Gk|_], NumVars, _, _, Gj, V, Type, N, Gj, V, Type, N) :-
  147.     function_number(Gk, K),
  148.     K < NumVars.
  149. select_vector([Gk|Gks], NumVars, NumGs, Gs,
  150.         GjIn, Vin, TypeIn, Nin, GjOut, Vout, TypeOut, Nout) :-
  151.     function_number(Gk, K),
  152.     K >= NumVars,
  153.     true_set(Gk, Tk),
  154.     select_vector(Tk, Gk, NumVars, NumGs, Gs,
  155.         GjIn, Vin, TypeIn, Nin, Gj, V, Type, N),
  156.     select_vector(Gks, NumVars, NumGs, Gs,
  157.         Gj, V, Type, N, GjOut, Vout, TypeOut, Nout).
  158.     
  159. % loop over vectors
  160. select_vector([], _, _, _, _, Gj, V, Type, N, Gj, V, Type, N).
  161. select_vector([V|Vs], Gk, NumVars, NumGs, Gs,
  162.         GjIn, Vin, TypeIn, Nin, GjOut, Vout, TypeOut, Nout) :-
  163.     vector_cover_type(NumVars, Gs, Gk, V, Type, N),
  164.     best_vector(GjIn, Vin, TypeIn, Nin,
  165.             Gk, V, Type, N,
  166.             Gj2, V2, Type2, N2),
  167.     select_vector(Vs, Gk, NumVars, NumGs, Gs,
  168.         Gj2, V2, Type2, N2, GjOut, Vout, TypeOut, Nout).
  169.  
  170. vector_cover_type(NumVars, Gs, Gj, Vector, Type, NumCovers) :-
  171.     immediate_predecessors(Gj, IPs),
  172.     conceivable_inputs(Gj, CIs),
  173.     false_set(Gj, Fj),
  174.     cover_type1(IPs, Gs, Vector, nf, 0, T, N),
  175.     cover_type2(CIs, Gs, NumVars, Fj, Vector, T, N, Type, NumCovers).
  176.  
  177. cover_type1([], _, _, T, N, T, N).
  178. cover_type1([I|IPs], Gs, V, TypeIn, Nin, TypeOut, Nout) :-
  179.     function(I, Gs, Gi),
  180.     true_set(Gi, Ti),
  181.     \+ set_member(V, Ti), !,
  182.     false_set(Gi, Fi),
  183.     (set_member(V, Fi) ->
  184.         max_type(TypeIn, cov, Type);
  185.         max_type(TypeIn, exp, Type)),
  186.     N is Nin + 1,
  187.     cover_type1(IPs, Gs, V, Type, N, TypeOut, Nout).
  188. cover_type1([_|IPs], Gs, V, TypeIn, Nin, TypeOut, Nout) :-
  189.     cover_type1(IPs, Gs, V, TypeIn, Nin, TypeOut, Nout).
  190.  
  191. cover_type2([], _, _, _, _, T, N, T, N).
  192. cover_type2([I|CIs], Gs, NumVars, Fj, V, TypeIn, Nin, TypeOut, Nout) :-
  193.     I < NumVars,
  194.     function(I, Gs, Gi),
  195.     false_set(Gi, Fi),
  196.     set_member(V, Fi), !,
  197.     max_type(TypeIn, var, Type),
  198.     N is Nin + 1,
  199.     cover_type2(CIs, Gs, NumVars, Fj, V, Type, N, TypeOut, Nout).
  200. cover_type2([I|CIs], Gs, NumVars, Fj, V, TypeIn, Nin, TypeOut, Nout) :-
  201.     I >= NumVars,
  202.     function(I, Gs, Gi),
  203.     true_set(Gi, Ti),
  204.     \+ set_member(V, Ti), !,
  205.     false_set(Gi, Fi),
  206.     (set_member(V, Fi) ->
  207.         (set_subset(Fj, Ti) ->
  208.             max_type(TypeIn, fcn, Type);
  209.             max_type(TypeIn, mcf, Type));
  210.         (set_subset(Fj, Ti) ->
  211.             max_type(TypeIn, exf, Type);
  212.             max_type(TypeIn, exmcf, Type))),
  213.     N is Nin + 1,
  214.     cover_type2(CIs, Gs, NumVars, Fj, V, Type, N, TypeOut, Nout).
  215. cover_type2([_|CIs], Gs, NumVars, Fj, V, TypeIn, Nin, TypeOut, Nout) :-
  216.     cover_type2(CIs, Gs, NumVars, Fj, V, TypeIn, Nin, TypeOut, Nout).
  217.  
  218. %  The best vector to cover is the one with worst type, or, if types
  219. %  are equal, with the least number of possible covers.
  220. best_vector(dummy, _, _, _, Gj2, V2, Type2, N2, Gj2, V2, Type2, N2) :- !.
  221. best_vector(Gj1, V1, Type1, N1, dummy, _, _, _, Gj1, V1, Type1, N1) :- !.
  222. best_vector(Gj1, V1, Type, N1, Gj2, _, Type, N2, Gj1, V1, Type, N1) :-
  223.     function_number(Gj1, J), function_number(Gj2, J),
  224.     N1 < N2, !.
  225. best_vector(Gj1, _, Type, N1, Gj2, V2, Type, N2, Gj2, V2, Type, N2) :-
  226.     function_number(Gj1, J), function_number(Gj2, J),
  227.     N1 >= N2, !.
  228. best_vector(Gj1, V1, Type, N1, Gj2, _, Type, _, Gj1, V1, Type, N1) :-
  229.     (Type = exp ; Type = var),
  230.     function_number(Gj1, J1), function_number(Gj2, J2),
  231.     J1 > J2, !.
  232. best_vector(Gj1, _, Type, _, Gj2, V2, Type, N2, Gj2, V2, Type, N2) :-
  233.     (Type = exp ; Type = var),
  234.     function_number(Gj1, J1), function_number(Gj2, J2),
  235.     J1 < J2, !.
  236. best_vector(Gj1, V1, Type, N1, Gj2, _, Type, _, Gj1, V1, Type, N1) :-
  237.     \+ (Type = exp ; Type = var),
  238.     function_number(Gj1, J1), function_number(Gj2, J2),
  239.     J1 < J2, !.
  240. best_vector(Gj1, _, Type, _, Gj2, V2, Type, N2, Gj2, V2, Type, N2) :-
  241.     \+ (Type = exp ; Type = var),
  242.     function_number(Gj1, J1), function_number(Gj2, J2),
  243.     J1 > J2, !.
  244. best_vector(Gj1, V1, Type1, N1, _, _, Type2, _, Gj1, V1, Type1, N1) :-
  245.     type_order(Type2, Type1), !.
  246. best_vector(_, _, Type1, _, Gj2, V2, Type2, N2, Gj2, V2, Type2, N2) :-
  247.     type_order(Type1, Type2), !.
  248.  
  249. max_type(T1, T2, T1) :- type_order(T1, T2), !.
  250. max_type(T1, T2, T2) :- \+ type_order(T1, T2), !.
  251.  
  252. %  Order of types
  253.  
  254. type_order(cov, exp).
  255. type_order(cov, var).
  256. type_order(cov, fcn).
  257. type_order(cov, mcf).
  258. type_order(cov, exf).
  259. type_order(cov, exmcf).
  260. type_order(cov, nf).
  261. type_order(exp, var).
  262. type_order(exp, fcn).
  263. type_order(exp, mcf).
  264. type_order(exp, exf).
  265. type_order(exp, exmcf).
  266. type_order(exp, nf).
  267. type_order(var, fcn).
  268. type_order(var, mcf).
  269. type_order(var, exf).
  270. type_order(var, exmcf).
  271. type_order(var, nf).
  272. type_order(fcn, mcf).
  273. type_order(fcn, exf).
  274. type_order(fcn, exmcf).
  275. type_order(fcn, nf).
  276. type_order(mcf, exf).
  277. type_order(mcf, exmcf).
  278. type_order(mcf, nf).
  279. type_order(exf, exmcf).
  280. type_order(exf, nf).
  281. type_order(exmcf, nf).
  282.  
  283. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  284.  
  285. %  Cover_vector will cover the specified vector and
  286. %  generate new circuit information.
  287. %  Using backtracking, all possible coverings are generated.
  288. %  The ordering of the possible coverings is approximately that
  289. %  given in Davidson's paper, but has been simplified.
  290.  
  291. cover_vector(NumVars, NumGsIn, GsIn, Gj, Vector, NumGsOut, GsOut) :-
  292.     immediate_predecessors(Gj, IPs),
  293.     conceivable_inputs(Gj, CIs),
  294.     vector_types(Type),
  295.     cover_vector(Type, IPs, CIs, Gj, Vector, NumVars, NumGsIn, GsIn,
  296.         NumGsOut, GsOut).
  297.     
  298. vector_types(var).
  299. vector_types(exp).
  300. vector_types(fcn).
  301. vector_types(mcf).
  302. vector_types(exf).
  303. vector_types(exmcf).
  304. vector_types(nf).
  305.  
  306. cover_vector(exp, [I|_], _, Gj, V, _, NumGs, GsIn, NumGs, GsOut) :-
  307.     function(I, GsIn, Gi),
  308.     true_set(Gi, Ti),
  309.     \+ set_member(V, Ti),
  310.     update_circuit(GsIn, Gi, Gj, V, GsIn, GsOut).
  311. cover_vector(exp, [_|IPs], _, Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut) :-
  312.     cover_vector(exp, IPs, _, Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut).
  313. cover_vector(var, _, [I|_], Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut) :-
  314.     I < NumVars,
  315.     function(I, GsIn, Gi),
  316.     false_set(Gi, Fi),
  317.     set_member(V, Fi),
  318.     update_circuit(GsIn, Gi, Gj, V, GsIn, GsOut).
  319. cover_vector(var, _, [_|CIs], Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut) :-
  320.     cover_vector(var, _, CIs, Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut).
  321. cover_vector(fcn, _, [I|_], Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut) :-
  322.     I >= NumVars,
  323.     function(I, GsIn, Gi),
  324.     false_set(Gi, Fi),
  325.     set_member(V, Fi),
  326.     true_set(Gi, Ti),
  327.     false_set(Gj, Fj),
  328.     set_subset(Fj, Ti),
  329.     update_circuit(GsIn, Gi, Gj, V, GsIn, GsOut).
  330. cover_vector(fcn, _, [_|CIs], Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut) :-
  331.     cover_vector(fcn, _, CIs, Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut).
  332. cover_vector(mcf, _, [I|_], Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut) :-
  333.     I >= NumVars,
  334.     function(I, GsIn, Gi),
  335.     false_set(Gi, Fi),
  336.     set_member(V, Fi),
  337.     true_set(Gi, Ti),
  338.     false_set(Gj, Fj),
  339.     \+ set_subset(Fj, Ti),
  340.     update_circuit(GsIn, Gi, Gj, V, GsIn, GsOut).
  341. cover_vector(mcf, _, [_|CIs], Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut) :-
  342.     cover_vector(mcf, _, CIs, Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut).
  343. cover_vector(exf, _, [I|_], Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut) :-
  344.     I >= NumVars,
  345.     function(I, GsIn, Gi),
  346.     false_set(Gi, Fi),
  347.     \+ set_member(V, Fi),
  348.     true_set(Gi, Ti),
  349.     \+ set_member(V, Ti),
  350.     false_set(Gj, Fj),
  351.     set_subset(Fj, Ti),
  352.     update_circuit(GsIn, Gi, Gj, V, GsIn, GsOut).
  353. cover_vector(exf, _, [_|CIs], Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut) :-
  354.     cover_vector(exf, _, CIs, Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut).
  355. cover_vector(exmcf, _, [I|_], Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut) :-
  356.     I >= NumVars,
  357.     function(I, GsIn, Gi),
  358.     false_set(Gi, Fi),
  359.     \+ set_member(V, Fi),
  360.     true_set(Gi, Ti),
  361.     \+ set_member(V, Ti),
  362.     false_set(Gj, Fj),
  363.     \+ set_subset(Fj, Ti),
  364.     update_circuit(GsIn, Gi, Gj, V, GsIn, GsOut).
  365. cover_vector(exmcf, _, [_|CIs], Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut) :-
  366.     cover_vector(exmcf, _, CIs, Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut).
  367. cover_vector(nf, _, _, Gj, V, NumVars, NumGsIn, GsIn, NumGsOut, GsOut) :-
  368.     NumGsOut is NumGsIn + 1,
  369.     false_set(Gj, Fj),
  370.     new_function_CIs(GsIn,
  371.         function(NumGsIn,Fj,[V],[],[],[],[],[]),
  372.         NumVars, Gs, Gi),
  373.     update_circuit(Gs, Gi, Gj, V, Gs, GsOut).
  374.  
  375.  
  376. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  377.  
  378. update_circuit([], _, _, _, _, []).
  379. update_circuit([function(K,Tk,Fk,CIk,IPk,ISk,Pk,Sk)|GsIn],
  380.         Gi, Gj, V, Gs,
  381.         [function(K,Tko,Fko,CIko,IPko,ISko,Pko,Sko)|GsOut]) :-
  382.     Gi = function(I,_,Fi,_,IPi,ISi,Pi,_),
  383.     Gj = function(J,_,Fj,_,_,_,_,Sj),
  384.     set_union([I], Pi, PiI),
  385.     set_union([J], Sj, SjJ),
  386.     (K = J ->
  387.         set_union(Tk, Fi, Tk2);
  388.         Tk2 = Tk),
  389.     (K = I ->
  390.         set_union(Tk2, Fj, Tk3);
  391.         Tk3 = Tk2),
  392.     ((set_member(K, IPi); set_member(K, ISi)) ->
  393.         set_union(Tk3, [V], Tko);
  394.         Tko = Tk3),
  395.     (K = I ->
  396.         set_union(Fk, [V], Fko);
  397.         Fko = Fk),
  398.     ((set_member(K, Pi); K = I) ->
  399.         set_difference(CIk, SjJ, CIk2);
  400.         CIk2 = CIk),
  401.     ((set_member(I, CIk), set_member(V, Fk)) ->
  402.         set_difference(CIk2, [I], CIk3);
  403.         CIk3 = CIk2),
  404.     (K = I ->
  405.         exclude_if_vector_in_false_set(CIk3, Gs, V, CIk4);
  406.         CIk4 = CIk3),
  407.     (K = J ->
  408.         set_difference(CIk4, [I], CIko);
  409.         CIko = CIk4),
  410.     (K = J ->
  411.         set_union(IPk, [I], IPko);
  412.         IPko = IPk),
  413.     (K = I ->
  414.         set_union(ISk, [J], ISko);
  415.         ISko = ISk),
  416.     (set_member(K, SjJ) ->
  417.         set_union(Pk, PiI, Pko);
  418.         Pko = Pk),
  419.     (set_member(K, PiI) ->
  420.         set_union(Sk, SjJ, Sko);
  421.         Sko = Sk),
  422.     update_circuit(GsIn, Gi, Gj, V, Gs, GsOut).
  423.  
  424. exclude_if_vector_in_false_set([], _, _, []).
  425. exclude_if_vector_in_false_set([K|CIsIn], Gs, V, CIsOut) :-
  426.     function(K, Gs, Gk),
  427.     false_set(Gk, Fk),
  428.     set_member(V, Fk), !,
  429.     exclude_if_vector_in_false_set(CIsIn, Gs, V, CIsOut).
  430. exclude_if_vector_in_false_set([K|CIsIn], Gs, V, [K|CIsOut]) :-
  431.     exclude_if_vector_in_false_set(CIsIn, Gs, V, CIsOut).
  432.  
  433.  
  434. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  435.  
  436. add_necessary_functions(NumVars, NumGsIn, GsIn, NumGsOut, GsOut) :-
  437.     add_necessary_functions(NumVars, NumVars, NumGsIn, GsIn,
  438.                     NumGsOut, GsOut).
  439.  
  440. add_necessary_functions(NumGs, _, NumGs, Gs, NumGs, Gs) :- !.
  441. add_necessary_functions(K, NumVars, NumGsIn, GsIn, NumGsOut, GsOut) :-
  442.     function(K, GsIn, Gk),
  443.     function_type(NumVars, NumGsIn, GsIn, Gk, nf, V), !,
  444.     false_set(Gk, Fk),
  445.     new_function_CIs(GsIn,
  446.         function(NumGsIn,Fk,[V],[],[],[],[],[]),
  447.         NumVars, Gs, Gl),
  448.     function(K, Gs, Gk1),
  449.     update_circuit(Gs, Gl, Gk1, V, Gs, Gs1),
  450.     NumGs1 is NumGsIn + 1,
  451.     K1 is K + 1,
  452.     add_necessary_functions(K1, NumVars, NumGs1, Gs1, NumGsOut, GsOut).
  453. add_necessary_functions(K, NumVars, NumGsIn, GsIn, NumGsOut, GsOut) :-
  454.     K1 is K + 1,
  455.     add_necessary_functions(K1, NumVars, NumGsIn, GsIn, NumGsOut, GsOut).
  456.  
  457. new_function_CIs(GsIn, function(L,Tl,Fl,_,IPl,ISl,Pl,Sl), NumVars,
  458.         [GlOut|GsOut], GlOut) :-
  459.     new_function_CIs(GsIn, L, Fl, NumVars, GsOut, [], CIlo),
  460.     GlOut = function(L,Tl,Fl,CIlo,IPl,ISl,Pl,Sl).
  461.     
  462. new_function_CIs([], _, _, _, [], CIl, CIl).
  463. new_function_CIs([function(K,Tk,Fk,CIk,IPk,ISk,Pk,Sk)|GsIn], L, Fl, NumVars,
  464.         [function(K,Tk,Fk,CIko,IPk,ISk,Pk,Sk)|GsOut], CIlIn, CIlOut) :-
  465.     set_intersection(Fl, Fk, []), !,
  466.     (K >= NumVars ->
  467.         set_union(CIk, [L], CIko);
  468.         CIko = CIk),
  469.     new_function_CIs(GsIn, L, Fl, NumVars, GsOut, [K|CIlIn], CIlOut).
  470. new_function_CIs([Gk|GsIn], L, Fl, NumVars, [Gk|GsOut], CIlIn, CIlOut) :-
  471.     new_function_CIs(GsIn, L, Fl, NumVars, GsOut, CIlIn, CIlOut).
  472.  
  473. function_type(NumVars, NumGs, Gs, Gk, Type, Vector) :-
  474.     true_set(Gk, Tk),
  475.     select_vector(Tk, Gk, NumVars, NumGs, Gs,
  476.         dummy, 0, nf, 999, _, Vector, Type, _).
  477.  
  478. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  479. %  Cost and constraint predicates:
  480.  
  481. % very simple bound for now
  482.  
  483. test_bounds(_, NumGs, _) :-
  484.     access(0, Bound),
  485.     NumGs < Bound.
  486.  
  487. update_bounds(_, NumGs, _) :-
  488.     set(0, NumGs).
  489.  
  490. % set and access for systems that don't support them
  491.  
  492. %:- dynamic '$set'/2.
  493. %set(N, A) :- (retract('$set'(N, _)); true), assert('$set'(N, A)), !.
  494. %access(N, A) :- '$set'(N,A), !.
  495.  
  496. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  497. %  Output predicates:
  498.  
  499. %  for now just dump everything
  500.  
  501. output_results(NumVars, NumGs, Gs) :-
  502.     NumGates is NumGs - NumVars,
  503.     write(NumGates), write(' gates'), nl,
  504.     write_gates(Gs), nl.
  505.  
  506. write_gates([]).
  507. write_gates([Gi|Gs]) :-
  508.     function_number(Gi, I),
  509.     write('gate #'), write(I), write(' inputs:   '),
  510.     immediate_predecessors(Gi, IPi),
  511.     write(IPi), nl,
  512.     write_gates(Gs).
  513.  
  514. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  515.  
  516. %  Retrieve the specified function from the function list.
  517. %  function(FunctionNumber, FunctionList, Function).
  518. function(I, [Gi|_], Gi) :- function_number(Gi, I), !.
  519. function(I, [_|Gs], Gi) :- function(I, Gs, Gi).
  520.  
  521. function_number(        function(I,_,_,_,_,_,_,_), I).
  522. true_set(               function(_,T,_,_,_,_,_,_), T).
  523. false_set(              function(_,_,F,_,_,_,_,_), F).
  524. conceivable_inputs(     function(_,_,_,CI,_,_,_,_), CI).
  525. immediate_predecessors( function(_,_,_,_,IP,_,_,_), IP).
  526. immediate_successors(   function(_,_,_,_,_,IS,_,_), IS).
  527. predecessors(           function(_,_,_,_,_,_,P,_), P).
  528. successors(             function(_,_,_,_,_,_,_,S), S).
  529.  
  530. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  531. %  Set operations assume that the sets are represented by an ordered list
  532. %  of integers.
  533.  
  534. set_union([],     [],     []).
  535. set_union([],     [X|L2], [X|L2]).
  536. set_union([X|L1], [],     [X|L1]).
  537. set_union([X|L1], [X|L2], [X|L3]) :-        set_union(L1, L2,     L3).
  538. set_union([X|L1], [Y|L2], [X|L3]) :- X < Y, set_union(L1, [Y|L2], L3).
  539. set_union([X|L1], [Y|L2], [Y|L3]) :- X > Y, set_union([X|L1], L2, L3).
  540.  
  541. set_intersection([],     [],     []).
  542. set_intersection([],     [_|_],  []).
  543. set_intersection([_|_],  [],     []).
  544. set_intersection([X|L1], [X|L2], [X|L3]) :-    set_intersection(L1, L2,     L3).
  545. set_intersection([X|L1], [Y|L2], L3) :- X < Y, set_intersection(L1, [Y|L2], L3).
  546. set_intersection([X|L1], [Y|L2], L3) :- X > Y, set_intersection([X|L1], L2, L3).
  547.  
  548. set_difference([],     [],     []).
  549. set_difference([],     [_|_],  []).
  550. set_difference([X|L1], [],     [X|L1]).
  551. set_difference([X|L1], [X|L2], L3) :-            set_difference(L1, L2,     L3).
  552. set_difference([X|L1], [Y|L2], [X|L3]) :- X < Y, set_difference(L1, [Y|L2], L3).
  553. set_difference([X|L1], [Y|L2], L3) :-     X > Y, set_difference([X|L1], L2, L3).
  554.  
  555. set_subset([],     _).
  556. set_subset([X|L1], [X|L2]) :-        set_subset(L1, L2).
  557. set_subset([X|L1], [Y|L2]) :- X > Y, set_subset([X|L1], L2).
  558.  
  559. set_member(X, [X|_]).
  560. set_member(X, [Y|T]) :- X > Y, set_member(X, T).
  561.